home *** CD-ROM | disk | FTP | other *** search
- page 66,132
- ;============================================================================
- ; ADDIT.COM adds a series of numbers captured from the display.
- ;
- ; Usage: ADDIT [/B][/U]
- ;
- ; B = Use Video BIOS calls
- ; U = Uninstall
- ;
- ; Revision History:
- ;
- ; Version 1.0 Initial Release
- ; Version 1.1 Bug fix
- ;
- ;============================================================================
- POPTIME equ 9 ;Allow 1/2 second to popup
-
- STACKSIZE equ 512 ;TSR stack
- MSGBOX_BUFFSIZE equ 1 * 132 * 2 ;Screen save buff for title
- HELPBOX_BUFFSIZE equ 5 * 132 * 2 ;Screen save buff for help
-
- MSGBOX_BUFFER equ offset end_of_resident
- ATTR_BUFFER equ MSGBOX_BUFFER + MSGBOX_BUFFSIZE
-
- ;----------------------------------------------------------------------------
- ; BIOS Data segment
- ;----------------------------------------------------------------------------
- bios_data segment at 40h
- org 17h
- shift_state db ? ;State of keyboard shift keys
- org 1Ah
- keybuff_head dw ? ;Start ptr for keyboard buff
- keybuff_tail dw ? ;End ptr for keyboard buff
-
- org 4Eh
- video_buffoff dw ? ;Offset of video buffer
- org 63h
- video_ioregs dw ? ;I/O addr of video controller
- org 80h
- keybuff_start dw ? ;Start ptr for keyboard buff
- keybuff_end dw ? ;End ptr for keyboard buff
- video_rows db ? ;Number of rows on the screen
- bios_data ends
-
- ;----------------------------------------------------------------------------
- ; ADDIT Code and Data segments
- ;----------------------------------------------------------------------------
- code segment
- assume cs:code
-
- org 2ch
- env_segment dw ? ;Word containing the segment
- ; of the program's env. block.
- org 80h
- command_tail db ? ;Offset of the command tail.
-
- org 100h
- prog: jmp initialize
- ;--------------------------------------------------------------------------- pushf
- ; Resident Data
- ;--------------------------------------------------------------------------- pushf
- program db 13,10
- program1 db "ADDIT 1.1 "
- copyright db "Copyright (c) 1992 Douglas Boling"
- program2 db 10,13
- db "First published in PC Magazine, Feburary 11, 1992"
- db 13,10,"$",1Ah
-
- def_marked_bw db 70h ;Default marked attr B/W
- def_text_bw db 70h ;Default text attr B/W
- def_number_bw db 79h ;Default number attr B/W
- def_neg_bw db 7Fh ;Default neg number attr B/W
- bw_segment dw 0B000h ;Segment of B/W video memory
-
- def_marked_clr db 70h ;Default marked attr Color
- def_text_clr db 71h ;Default text attr Color
- def_number_clr db 7Eh ;Default number attr Color
- def_neg_clr db 74h ;Default neg number attr Color
- clr_segment dw 0B800h ;Segment of color video memory
-
- attr_buffsize dw 1024 ;Size of attribute buffer
- helpbox_buff dw 0 ;Pointer to helpbox buffer
- res_stack dw 0 ;Stack ptr when resident
-
- indos_ptr dd -1 ;Pointer to INDOS flag
- criterr_ptr dd -1 ;Pointer to DOS crit err flag
-
- int08h dd -1 ;Int 2f vector (Timer)
- int09h dd -1 ;Int 09 vector (Keyboard HW)
- int10h dd -1 ;Int 10 vector (Video BIOS)
- int13h dd -1 ;Int 13 vector (Disk BIOS)
- int28h dd -1 ;Int 28 vector (DOS Idle)
- int2Fh dd -1 ;Int 2F vector (DOS Multiplex)
-
- int08_active db 0 ;Interrupt active flag
- int09_active db 0 ;Interrupt active flag
- int10_active db 0 ;Interrupt active flag
- int13_active db 0 ;Interrupt active flag
- int28_active db 0 ;Interrupt active flag
- int2F_active db 0 ;Interrupt active flag
- main_active db 0 ;TSR active flag
-
- saved_ss dw 0
- saved_sp dw 0
-
- hotshift db 0ah ;Shift condition for popup
- popflag db 0 ;Go active counter
-
- keycodes db 3bh,4eh,0dh,51h,49h,4fh,47h,48h,50h,74h,73h,4bh,4dh
- keycodes_end = $
-
- keyjmp_table dw offset cursor_rt ;Index into key routines are
- dw offset cursor_lt ; inverse of order of
- dw offset cursor_clt ; keycode array.
- dw offset cursor_crt
- dw offset cursor_dn
- dw offset cursor_up
- dw offset cursor_home ;Home
- dw offset cursor_end ;End
- dw offset cursor_top ;Page Up
- dw offset cursor_bottom ;Page Down
- dw offset addmarked ;=/+ key
- dw offset addmarked ;keypad +
- dw offset showhelp ;F1
-
- addmarked_tbl dw offset add_digit ;Digit after digit
- dw offset setdec ;Period after digit
- dw offset chkcomma ;Comma after digit
- dw offset setneg ;Dash after digit
- dw offset termnumber ;Char after digit
- dw offset add_digit ;Digit after char
- dw offset setdec ;Period after char
- dw offset termnumber ;Comma after char
- dw offset setneg1 ;Dash after char
- dw offset termnumber ;Char after char
-
- summsg db "Sum:",0
- pastemsg db "Number too long to paste",0
- helptag db "F1 for Help",0
- no_help db 0 ;Blocks help msg
- ; 1234567891123456789212345678931234567894
- helpmsg1 db " <Cursor> keys delete box/move cursor "
- db " <Shift><Cursor> keys size box",0
- helpmsg2 db " <Home> Move to start of line "
- db " <End> Move to end of line",0
- helpmsg3 db " <Pg Up> Move to top of screen "
- db " <Pg Dn> Move to bot of screen",0
- helpmsg4 db " <+> Add numbers found in box "
- db " <P> Paste sum into application",0
- helpmsg5 db " <Esc> Exit the program",0
-
- overflowmsg db "Overflow",0
- ;
- ;Screen variables
- ;
- BIOSFlag db 0 ;1 = Use Vid BIOS calls
- video_ptr label dword
- video_offset dw 0 ;Offset of video memory
- video_seg dw 0 ;Segment of video memory
-
- marked_attr db 0 ;Screen attr for marked area
- text_attr db 0 ;Attribute for msg box text
- number_attr db 0 ;Attribute to mark numbers
- negative_attr db 0 ;Attribute to mark neg numbers
-
- cursor_pos dw 0 ;Cursor position at popup
- cursor_type dw 0 ;Cursor shape at popup
-
- screen_page db 0 ;Active video page
- screen_size label word
- screen_cx db 0 ;Screen columns
- screen_cy db 0 ;Screen rows
-
- marked_pos1 label word
- marked_x1 db 0 ;Marked area starting column
- marked_y1 db 0 ;marked area starting row
- marked_pos2 label word
- marked_x2 db 0 ;Marked area ending column
- marked_y2 db 0 ;marked area ending row
-
- oldmarked_pos1 label word
- oldmarked_x1 db 0 ;Marked area starting row
- oldmarked_y1 db 0 ;marked area starting column
- oldmarked_pos2 label word
- oldmarked_x2 db 0 ;Marked area columns
- oldmarked_y2 db 0 ;marked area rows
-
- boxactive db 0 ;Flag for message box
- ;
- ;Variables used in the addition routines.
- ;
- base dw 10 ;base 10
- sum_num dw 3 dup (0)
- sum_exp db 0
- sum_sign db 0
-
- curr_num dw 3 dup (0)
- curr_exp db 0
- curr_sign db 0
-
- sum_overflow db 0
- decimal_flag db 0
- curr_num_active db 0
- last_char db 0
-
- ;============================================================================
- ; VIDEOINT processes BIOS video services interrupt (Int 10h)
- ;============================================================================
- videoint proc far
- assume cs:code,ds:nothing,es:nothing
- inc cs:int10_active
- pushf
- call cs:[int10h] ;Call old int
- dec cs:int10_active
- iret ;Return
- videoint endp
-
- ;============================================================================
- ; DISKINT processes BIOS disk services interrupt (Int 13h)
- ;============================================================================
- diskint proc far
- assume cs:code,ds:nothing,es:nothing
- inc cs:int13_active
- pushf
- call cs:[int13h] ;Call old int
- pushf
- dec cs:int13_active
- popf
- ret 2 ;Return preserving flags
- diskint endp
-
- ;============================================================================
- ; TIMERINT processes timer interrupt (Int 08h)
- ;============================================================================
- timerint proc far
- assume cs:code,ds:nothing,es:nothing
- pushf
- call cs:[int08h] ;Call old int 8
- push ds
- push cs
- pop ds
- assume ds:code
-
- cmp int08_active,0 ;See if we are in this
- jne timerint_exit1 ; routine already
- inc int08_active
-
- cmp popflag,0 ;See if we need to try to
- jne timer_check ; pop up
- timerint_exit:
- dec int08_active
- timerint_exit1:
- pop ds
- iret ;Return
- timer_check:
- push ax
- call check_system ;See if system OK to pop up
- or ax,ax
- je timerint_1
-
- or ah,ah
- je timerint_dec
- push ax
- push bx
- mov ax,0e07h
- mov bx,0
- int 10h
- pop bx
- pop ax
- jmp timerint_dec
- timerint_1:
-
- call main ;Call the TSR
- mov popflag,1
- timerint_dec:
- dec popflag
- pop ax
- jmp short timerint_exit
- timerint endp
-
- ;============================================================================
- ; KEYINT processes keyboard interrupts (Int 09h)
- ;============================================================================
- keyint proc far
- assume cs:code,ds:nothing,es:nothing
- pushf
- call cs:[int09h] ;Call old int 9
-
- push ax
- push ds
- mov ax,40h
- mov ds,ax ;Set ES to bios data segment
- assume ds:bios_data
- mov al,ds:[shift_state]
- and al,0fh ;Mask lock bits
- cmp al,cs:[hotshift]
- pop ds
- pop ax
- je keyint_hotkey
- keyint_exit:
- iret ;Return
- keyint_hotkey:
- mov cs:popflag,POPTIME ;Set timer to pop up
- jmp short keyint_exit
- keyint endp
-
- ;============================================================================
- ; IDLEINT processes DOS Idle interrupt (Int 28h)
- ;============================================================================
- idleint proc far
- assume cs:code,ds:nothing,es:nothing
- pushf
- call cs:[int28h] ;Call old int
- push ds
- push cs
- pop ds
- assume ds:code
- cmp int28_active,0 ;See if we are in this
- jne idleint_exit1 ; routine already
- inc int28_active ;Set int active flag
- cmp popflag,0 ;See if we need to try to
- jne idle_check ; pop up
- idleint_exit:
- dec int28_active ;Set int active flag
- idleint_exit1:
- pop ds
- iret ;Return
- idle_check:
- push ax
- call check_system ;See if OK to pop up. Ignore
- or al,al ; INDOS since in idle.
- jne idleint_1
- mov popflag,0 ;Clear popup flag
- call main ;Call the TSR
- idleint_1:
- pop ax
- jmp short idleint_exit
- idleint endp
-
- ;--------------------------------------------------------------------------- pushf
- ; Check System Determines if the system is in a state compatible with TSRs
- ; Exit: AL - ORed flags for DOS Idle OK
- ; AH - State of INDOS flag
- ;--------------------------------------------------------------------------- pushf
- check_system proc near
- assume cs:code,ds:code,es:nothing
- push bx
- push ds
- xor ax,ax
- or al,int10_active ;Check BIOS video int
- or al,int13_active ;Check BIOS disk int
- ; or al,int16_active ;Check BIOS keyboard int
- lds bx,criterr_ptr ;Check DOS critical error
- or al,byte ptr ds:[bx] ; flag.
- lds bx,cs:indos_ptr ;Check INDOS flag
- mov ah,byte ptr ds:[bx]
- check_sys_exit:
- pop ds
- pop bx
- ret
- check_system endp
-
- ;============================================================================
- ; MAIN this is the main body of the TSR
- ;============================================================================
- main proc near
- assume cs:code,ds:code,es:nothing
- cmp main_active,0 ;See if already active
- jne main_exit
- cli
-
- inc main_active
- mov [saved_sp],sp ;Save old stack pointer
- mov [saved_ss],ss
-
- mov ax,cs ;Set ss:sp to internal stack
- mov ss,ax
- mov sp,res_stack
- sti ;Enable interrupts
- cld ;Set string direction UP
-
- push bx
- push cx
- push dx
- push di
- push si
- push bp
- push es
- mov ah,0fh ;Get display mode
- int 10h
- cmp al,7
- je main_1 ;Pop up only if in text mode.
- cmp al,4
- jb main_1
- main_exit1:
- pop es
- pop bp
- pop si
- pop di
- pop dx
- pop cx
- pop bx
-
- cli
- mov ss,[saved_ss] ;Restore old stack
- mov sp,[saved_sp]
- dec main_active
- main_exit:
- ret
- main_1:
- mov byte ptr no_help,0 ;Enable help message
- cmp ah,80
- jb main_exit1
- mov screen_page,bh ;Save active video page
- mov screen_cx,ah ;Save screen columns
-
- mov ah,3 ;Get cursor position
- int 10h
- mov cursor_pos,dx ;Save cursor information
- mov cursor_type,cx
- cmp dh,0 ;If on top line, move down 1
- jne main_11 ; to miss banner.
- inc dh
- main_11:
- mov marked_pos1,dx ;Save initial cursor position
- mov ax,40h
- mov es,ax ;Set ES to bios data segment
- assume es:bios_data
- mov ah,12h ;Determine if CGA by checking
- mov bl,10h ; for EGA compatibility
- int 10h
- mov al,24 ;CGA, only 25 rows on screen
- cmp bl,10h
- je main_2
-
- mov al,es:video_rows ;Get number of rows on screen
- main_2:
- mov screen_cy,al ;Save screen rows
- mov ax,es:video_buffoff ;Copy ptr to video memory
- mov video_offset,ax
-
- mov ax,marked_pos1 ;Copy starting pos to ending
- mov marked_pos2,ax ; pos to zero block.
- mov oldmarked_pos1,ax
- mov oldmarked_pos2,ax
-
- test es:video_ioregs,40h ;See if color or monochrome
- jne main_colorvid
-
- mov si,offset def_marked_bw ;Point to B/W parameters
- jmp short main_3
- main_colorvid:
- mov si,offset def_marked_clr ;Point to color parameters
- main_3:
- push ds
- pop es
- assume es:code
-
- mov di,offset marked_attr ;Copy default attributes
- movsw
- movsw
- lodsw ;Get Video buffer segment
- mov video_seg,ax
-
- mov ah,1 ;Hide the cursor by changing
- mov cx,200h ; the size of the cursor
- int 10h
-
- call init_attrlist ;Initialize attr save list
- jc main_end1
-
- mov dx,marked_pos1 ;Mark initial cursor where
- call getchar ; the old cursor was
- mov ah,marked_attr ;Mark cursor position on
- call putchar ; screen.
- main_loop:
- cmp boxactive,1 ;If box active, don't reprint
- je main_4 ; the box.
-
- mov al,marked_y2 ;If cursor on top line, don't
- or al,marked_y2 ; print the title box.
- je main_4
- call msgbox ;Draw title box
- main_4:
- call getkey ;Wait for a key
- cmp al,27 ;If ESC, end.
- je main_end
- cmp ah,25 ;If 'p' paste and exit
- je main_paste
- mov al,ah ;Copy scan code
- main_6:
- mov di,offset keycodes
- mov cx,offset keycodes_end - offset keycodes
- repne scasb
- jne main_loop
- shl cx,1 ;Convert key num into jump
- mov bx,cx ; table index.
- mov ax,marked_pos2 ;Preload parameters into regs
- mov cx,screen_size ; to save code
- call [keyjmp_table+bx] ;Call key routine
- jmp short main_loop
- main_paste:
- call paste ;Paste to keyboard buffer
- main_end:
- call clearmarked ;Restore attributes
- call clearbox ;Delete title box
- main_end1:
- mov ah,1 ;Set cursor type
- mov cx,cursor_type
- mov bh,screen_page
- int 10h
- mov ah,2 ;Set cursor position
- mov dx,cursor_pos
- int 10h
- jmp main_exit1
- main endp
-
- ;-----------------------------------------------------------------------------
- ; CURSOR KEYS Handles the actions of the cursor keys as the user uses them
- ; to mark the selected area.
- ; Entry: AL - marked_x2
- ; AH - marked_y2
- ; CL - screen_cx
- ; CH - screen_cy
- ;-----------------------------------------------------------------------------
- cursor_keys proc near
-
- ; CURSOR HOME Moves the cursor to the left most column
- cursor_home:
- xor al,al ;Zero current column
- jmp short cursor_1
- ; CURSOR END Moves the cursor to the right most column
- cursor_end:
- mov al,cl ;Set Cur column to screen cols
- dec al
- jmp short cursor_1
- ; CURSOR TOP Moves the cursor to the top row
- cursor_top:
- mov ah,1 ;Move to line 1 to avoid
- jmp short cursor_1 ; title erase
- ; CURSOR END Moves the cursor to the bottom row
- cursor_bottom:
- mov ah,ch ;Set Cur Row to screen rows
- jmp short cursor_1
- ; CURSOR UP Moves the marked orgin up one row
- cursor_up:
- or ah,ah
- je cursor_1
- dec ah
- jmp short cursor_1
- ; CURSOR DN Moves the marked orgin down one row
- cursor_dn:
- cmp ah,ch
- je cursor_1
- inc ah
- jmp short cursor_1
- ; CURSOR CLT Moves the marked orgin left 8 columns
- cursor_clt:
- sub al,8
- jae cursor_1
- xor al,al
- jmp short cursor_1
- ; CURSOR CRT Moves the marked orgin right 8 columns
- cursor_crt:
- add al,8
- dec cl
- cmp al,cl
- jb cursor_1
- mov al,cl
- jmp short cursor_1
- ; CURSOR LT Moves the marked orgin left one col
- cursor_lt:
- or al,al
- je cursor_1
- dec al
- jmp short cursor_1
- ; CURSOR RT Moves the marked orgin right one col
- cursor_rt:
- dec cl
- cmp al,cl
- jae cursor_1
- inc al
- cursor_1:
- mov marked_pos2,ax ;Save new position
- push ax
- mov ah,2 ;Get shift state
- int 16h
- and al,3
- pop ax
- je cursor_11
- mov si,offset sum_num ;If changing the size of the
- call clear_number ; box, clear the sum.
- inc boxactive
- jmp short cursor_2
- cursor_11:
- mov marked_pos1,ax ;Not shifted, set points equal
- cursor_2:
- or ah,ah ;If cursor on top line, clear
- jne cursor_3 ; title box so user can see
- call clearbox ; what is on top line.
- cursor_3:
- call drawmarked
- ret
- cursor_keys endp
-
- ;-----------------------------------------------------------------------------
- ; PASTE Clears the keyboard buffer, then copys the sum into the buffer.
- ; Entry: SI - Points to ASCIIZ string to paste into keyboard buffer.
- ;-----------------------------------------------------------------------------
- paste proc near
- push es
- mov di,offset command_tail ;Point buffer
- mov si,offset sum_num
- push di
- call hex2asc ;Convert sum to ASCII
- pop si
- inc si ;Move past attribute
- mov cx,di ;Compute length of number
- sub cx,si
-
- cmp sum_overflow,0
- jne paste_exit
- mov ax,bios_data
- mov es,ax
- assume es:bios_data
- cli ;No interrupts
- mov di,es:[keybuff_start] ;Get ptr to buffer offset
- mov bx,es:[keybuff_end] ;Get ptr to end of buffer
- push bx
- sub bx,di
- shr bx,1
- cmp cx,bx
- pop bx
- ja paste_overflow
- sub bx,2
- mov es:[keybuff_head],di ;Clear buffer by setting
- mov es:[keybuff_tail],di ; pointers equal.
- paste_1:
- lodsb ;Get character
- or al,al ;See if end of string
- je paste_done
- paste_2:
- call getscan ;Get scan code for char
- stosw ;Stuff in keyboard buffer
- cmp di,bx ;See if buffer full
- jb paste_1 ;No, continue
- mov es:[keybuff_tail],di
- paste_overflow:
- sti
- mov si,offset pastemsg ;If number longer than the
- mov dx,39 ; keyboard buffer print
- mov ah,negative_attr ; message to warn user.
- call writestr1
- call getkey
- paste_done:
- mov es:[keybuff_tail],di
- sti
- paste_exit:
- pop es
- ret
- paste endp
-
- ;-----------------------------------------------------------------------------
- ; GETSCAN Returns the keyboard scan code for a limit set of ASCII characters
- ; Entry: AL - ASCII character
- ; Exit: AH - Scan code
- ;-----------------------------------------------------------------------------
- xlate_keys db 27,"1234567890-,."
- xlate_keys_end = $
- xlate_scan db 52,51,12,11,10,9,8,7,6,5,4,3,2,1 ;Rev of ASCII table
- getscan proc near
- push di
- push es
- mov cx,cs
- mov es,cx
- mov cx,offset xlate_keys_end - offset xlate_keys
- mov di,offset xlate_keys
- repne scasb
- mov di,cx
- mov ah,[xlate_scan+di]
- pop es
- pop di
- ret
- getscan endp
-
- ;-----------------------------------------------------------------------------
- ; DRAWMARKED Displays the marked area by changing the screen attributes
- ; inside the marked area.
- ;-----------------------------------------------------------------------------
- drawmarked proc near
- push es
-
- mov ax,marked_pos1
- mov dx,marked_pos2
- cmp dx,oldmarked_pos2
- jne drawmarked_1
-
- cmp ax,oldmarked_pos1
- je drawmarked_exit
- drawmarked_1:
- mov bx,offset marked_pos1
- mov cx,4
- drawmarked_2:
- call find_min ;AX = upper left corner
- call find_max ;DX = lower right corner
- add bx,2
- loop drawmarked_2
- drawmarked_7:
- sub dx,ax ;Compute size of area
-
- xor cx,cx
- mov cl,dl ;Copy column count
- mov si,cx
- inc si
- mov cl,dh ;Copy row count
- inc cx
- mov dx,ax ;Copy starting row, column
- drawmarked_8:
- push cx ;Save row count
- push dx ;Save cursor position
- mov cx,si ;Get column count
- drawmarked_9:
- mov bx,offset marked_pos1
- call chk_inwin
- mov ah,al ;Save in marked area flag
-
- mov bx,offset oldmarked_pos1
- call chk_inwin
-
- cmp ah,al ;See if in or out of both
- je drawmarked_11 ; areas. If so, no change.
-
- push ax ;Save in-window flags
- call getchar
- pop bx
- or bh,bh ;See if in marked area
- je drawmarked_10
-
- mov ah,marked_attr ;Mark character
- call putchar
-
- jmp short drawmarked_11
- drawmarked_10:
- call get_attr ;Get saved screen attribute
- call putchar ;Restore attribute
- drawmarked_11:
- inc dl
- loop drawmarked_9
-
- pop dx
- pop cx
- inc dh
- loop drawmarked_8
-
- mov ax,marked_pos1 ;Update old pointers
- mov oldmarked_pos1,ax
- mov ax,marked_pos2
- mov oldmarked_pos2,ax
- drawmarked_exit:
- pop es
- ret
- drawmarked endp
-
- ;-----------------------------------------------------------------------------
- ; CLEARMARKED Restores the marked area to its original screen attributes
- ;-----------------------------------------------------------------------------
- clearmarked proc near
- assume ds:code
- mov bx,offset marked_pos1
- call compute_box
- sub ax,dx
- xor cx,cx
- mov cl,al
- mov si,cx ;Save column count
- inc si
- mov cl,ah
- inc cx
- clearmarked_3:
- push cx
- push dx
- mov cx,si
- clearmarked_4:
- call getchar
- call get_attr ;Get saved screen attribute
- call putchar
- inc dl
- loop clearmarked_4
-
- pop dx
- pop cx
- inc dh
- loop clearmarked_3
- clearmarked_exit:
- ret
- clearmarked endp
-
- ;-----------------------------------------------------------------------------
- ; ADDMARKED Finds numbers in marked area, marks them, then sums them.
- ;-----------------------------------------------------------------------------
- addmarked proc near
- assume ds:code
-
- mov si,offset sum_num ;Zero sum
- call clear_number
- mov di,si
- mov si,offset curr_num ;Zero current number
- call clear_number
-
- xor al,al
- mov decimal_flag,al ;Zero other flags
- mov sum_overflow,al
- mov curr_sign,al
- mov curr_num_active,al
-
- mov bx,offset marked_pos1 ;Compute dim of marked box
- call compute_box
- sub ax,dx ;Compute size of box
- xor cx,cx
- mov cl,al
- inc cx
- mov bp,cx ;BP = column count
- mov cl,ah
- inc cx ;CX = row count
- addmarked_loop1:
- push cx
- push dx
- mov cx,bp ;Get column count
- addmarked_loop2:
- push cx
- call getchar ;Read char from screen
- call isnum ;See if character is a number
- mov bl,ch
- mov bh,ch
- xchg last_char,bh ;Change routine called
- or bh,bh ; depending on if the
- je addmarked_3 ; pervious char was a digit.
- add bl,5
- addmarked_3:
- xor bh,bh
- shl bx,1
- push ax
- call [addmarked_tbl+bx]
- pop ax
- cmp curr_num_active,0 ;See if we need to mark the
- je addmarked_4 ; character
- call marknum
- addmarked_4:
- pop cx
- inc dl ;Inc Column
- loop addmarked_loop2
-
- call termnumber ;Number ends at boundry
- pop dx
- pop cx
- inc dh ;Inc Row
- loop addmarked_loop1
- inc boxactive ;Force box to be redrawn
- addmarked_exit:
- ret
- addmarked endp
-
- ;-----------------------------------------------------------------------------
- ; ADDDIGIT Adds digit to current number
- ; Entry: SI - Pointer to current number
- ; DI - Pointer to sum number
- ;-----------------------------------------------------------------------------
- add_digit proc near
- mov bl,decimal_flag ;If sign or fraction flags set
- add bl,curr_sign ; back up to mark the leading
- je add_digit_1 ; characters
- call markprev ;Mark preceding char
- add_digit_1:
- inc curr_num_active ;Digit found
- mov bx,base
- call mul_number ;Multiply number by BASE
- jo add_digit_3
-
- cmp decimal_flag,0 ;If in fraction, inc exponent
- je add_digit_2
- inc curr_exp
- add_digit_2:
- add [si],cx ;Add new digit to number
- adc word ptr [si+2],0
- adc word ptr [si+4],0
- jno short add_digit_exit
- add_digit_3:
- inc sum_overflow ;Set overflow flag
- add_digit_exit:
- ret
- add_digit endp
-
- ;-----------------------------------------------------------------------------
- ; SETDEC Process decimal point after character
- ; Entry: SI - Pointer to current number
- ; DI - Pointer to sum number
- ;-----------------------------------------------------------------------------
- setdec proc near
- cmp decimal_flag,0 ;If decimal flag already found
- je setdec_1 ; the period terminates the
- call termnumber ; current number.
- jmp short setdec_exit
- setdec_1:
- mov decimal_flag,1 ; current number.
- setdec_exit:
- ret
- setdec endp
-
- ;-----------------------------------------------------------------------------
- ; CHKCOMMA Process commas
- ; Entry: SI - Pointer to current number
- ; DI - Pointer to sum number
- ;-----------------------------------------------------------------------------
- chkcomma proc near
- cmp decimal_flag,0 ;If decimal flag already found
- je chkcomma_exit ; the comma terminates the
- call termnumber ; current number.
- chkcomma_exit:
- ret
- chkcomma endp
-
- ;-----------------------------------------------------------------------------
- ; SETNEG Process dash after character
- ;-----------------------------------------------------------------------------
- setneg proc near
- call termnumber ;If num active, terminate it
- setneg1:
- mov curr_sign,1 ;Set sign bit.
- ret
- setneg endp
-
- ;-----------------------------------------------------------------------------
- ; TERMNUMBER Process character after character
- ; Entry: SI - Pointer to current number
- ; DI - Pointer to sum number
- ;-----------------------------------------------------------------------------
- termnumber proc near
- cmp curr_num_active,0 ;See if a number is active
- je termnum_clear
-
- push di ;Save original pointers
- push si
- mov al,[di+6] ;Get destination exponent
- sub al,[si+6] ;Compare to source exponent
- je termnum_2 ;If equal power, skip shift.
- ja termnum_1 ;If dest exp less, shift
- xchg si,di ; destination instead of
- neg al ; the source.
- termnum_1:
- add [si+6],al ;Change exponent
- xor ah,ah
- mov cx,ax
- mov bx,base
- termnum_11:
- call mul_number ;Mul number by the base
- jo termnum_2 ; raised to the power of the
- loop termnum_11 ; of the exponent.
- termnum_2:
- pop si ;Restore original pointers
- pop di
- jo termnum_overflow
-
- call add_number ;Add numbers together
- jno termnum_3
- termnum_overflow:
- inc sum_overflow ;Set overflow flag
- termnum_3:
- call clear_number ;Zero current number
- termnum_clear:
- xor al,al
- mov curr_num_active,al ;Terminate number
- mov decimal_flag,al ;Zero fraction flag
- mov curr_sign,al ;Clear sign
- termnum_exit:
- ret
- termnumber endp
-
- ;-----------------------------------------------------------------------------
- ; ISNUM - Determines if a character is a number, a break character, or a
- ; character to be ignored
- ; Entry: AL - character
- ; Exit: CL - Number, if character is a number
- ; CH - 0 if number, 1 if decimal point, 2 if comma, 3 if a dash,
- ; 4 if anything else.
- ;-----------------------------------------------------------------------------
- isnum proc near
- mov ch,3 ;Use AH as char type flag
- mov cl,al
- cmp cl,'-' ;Is char a dash?
- je isnum_1
- dec ch
- cmp cl,',' ;Is char a comma?
- je isnum_1
- dec ch
- cmp cl,'.' ;Is char a decimal point?
- je isnum_1
- dec ch
- sub cl,'0' ;Convert char to number
- jb isnum_no
- cmp cl,9
- ja isnum_no
- isnum_1:
- clc
- isnum_exit:
- ret
- isnum_no:
- mov ch,4
- jmp short isnum_exit
- isnum endp
-
- ;-----------------------------------------------------------------------------
- ; MARKNUM - Sets the attribute of a number on the screen
- ; Entry: AL - character on screen
- ; DH,DL - Current row/column
- ;-----------------------------------------------------------------------------
- marknum proc near
- mov ah,number_attr ;Change attribute to indicate
- cmp curr_sign,0 ; that a number has been
- je marknum_1 ; found.
- mov ah,negative_attr
- marknum_1:
- call putchar ;Write attribute
- ret
- marknum endp
-
- ;-----------------------------------------------------------------------------
- ; MARKPREV - Sets the attribute of the character before the current char
- ; Entry: BL - Number of prev characters to mark
- ; DH,DL - Current row/column
- ;-----------------------------------------------------------------------------
- markprev proc near
- dec dl ;Back up and read prev char
- dec bl ;Recursively call markprev
- je markprev_1 ; to mark the proper number
- call markprev ; of characters.
- markprev_1:
- push ax
- call getchar
- call marknum ;Mark char
- inc dl ;Go back to original char
- pop ax
- ret
- markprev endp
-
- ;-----------------------------------------------------------------------------
- ; MULNUMBER - Multiplys a number pointed to by SI by the number in BX
- ; Entry: SI pointer to number
- ; BX number
- ; Exit: OF - set if overflow
- ;-----------------------------------------------------------------------------
- mul_number proc near
- push ax
- push dx
- mov ax,[si+4]
- imul bx ;Mul upper word
- jo mulnum_exit
- mov [si+4],ax
-
- mov ax,[si+2]
- mul bx ;Mul mid word
- add [si+4],dx
- jo mulnum_overflow
- mov [si+2],ax
-
- mov ax,[si]
- mul bx ;Mul lower word
- add [si+2],dx
- adc word ptr [si+4],0
- jo mulnum_overflow
- mov [si],ax
- clc
- mulnum_exit:
- pop dx
- pop ax
- ret
- mulnum_overflow:
- stc
- jmp short mulnum_exit
- mul_number endp
-
- ;-----------------------------------------------------------------------------
- ; ADDNUMBER - Adds two numbers pointed to by SI and DI
- ; Entry: SI pointer to first number
- ; DI pointer to second number
- ; Exit: OF - set if overflow
- ;-----------------------------------------------------------------------------
- add_number proc near
- cmp curr_sign,0 ;If the source is negitive,
- je addnum_1 ; 2's compliment the number.
- call neg_number
- addnum_1:
- push si
- lodsw ;Get low source word
- add [di],ax ;Add to dest low word
- lodsw ;Get mid source word
- adc [di+2],ax
- lodsw ;Get high source word
- adc [di+4],ax ;Add to dest high word
- pop si
- ret
- add_number endp
-
- ;-----------------------------------------------------------------------------
- ; NEGNUMBER - Performs a two'w compliment on the number
- ; Entry: SI pointer to number structure
- ;-----------------------------------------------------------------------------
- neg_number proc near
- not word ptr [si] ;2's compliment the number
- not word ptr [si+2]
- not word ptr [si+4]
- xor ax,ax
- stc
- adc word ptr [si],ax
- adc word ptr [si+2],ax
- adc word ptr [si+4],ax
- ret
- neg_number endp
-
- ;-----------------------------------------------------------------------------
- ; CLRNUMBER - Clears the a number
- ; Entry: SI pointer to number structure
- ;-----------------------------------------------------------------------------
- clear_number proc near
- push ax
- push di
- mov di,si
- xor ax,ax
- stosw ;Clear low word
- stosw ;Clear mid word
- stosw ;Clear high word
- stosw ;Clear flags
- pop di
- pop ax
- ret
- clear_number endp
-
- ;-----------------------------------------------------------------------------
- ; GET ATTR Gets a saved attribute in the attribute buffer for a given
- ; cursor location.
- ; Entry: DX - Row, Column of character
- ; Exit: AH - Attribute
- ;-----------------------------------------------------------------------------
- get_attr proc near
- push cx
- push dx
- push si
- push ax
- call compute_offset ;Get count into buffer
- mov si,ATTR_BUFFER
- xor ax,ax
- mov dx,ax
- get_attr_1:
- lodsb ;Get count byte
- inc si
- or al,al
- je get_attr_exit
- sub cx,ax
- jae get_attr_1
- mov dh,[si-1] ;Get attribute
- get_attr_exit:
- pop ax
- mov ah,dh ;Copy attribute
- pop si
- pop dx
- pop cx
- ret
- get_attr endp
-
- ;-----------------------------------------------------------------------------
- ; INIT ATTRLIST Initializes the attribute list
- ;-----------------------------------------------------------------------------
- init_attrlist proc near
- assume ds:code
- mov bx,screen_size ;Get size of screen
- inc bh
- inc bh
- xor ax,ax
- mov dx,ax ;Start at top left corner
- mov cx,ax
- xchg bh,cl ;CX-Col count, BX-Row cnt
- mov si,bx
- mov di,ATTR_BUFFER ;Get pointer to buffer
- call getchar
- mov bh,ah
- mov bl,0
- init_attrlist_1:
- push cx
- push dx
- mov cx,si ;Get number of columns
- init_attrlist_2:
- call getchar ;Read attribute
- cmp bh,ah ;Compare attributes
- jne init_attrlist_newblk ;If different write block
- inc bl ;Incriment count
- cmp bl,-1 ;If count full, write block
- je init_attrlist_newblk
- mov bh,ah ;Copy attribute value
- init_attrlist_3:
- inc dl ;Next column
- loop init_attrlist_2
- pop dx
- pop cx
- inc dh ;Next row
- loop init_attrlist_1
- clc
- init_attrlist_exit:
- ret
- init_attrlist_newblk:
- mov ds:[di],bx ;Write old block to list
- inc di ;Update ptr
- inc di
- mov bl,1 ;New count
- mov bh,ah ;Copy new attribute
- cmp di,helpbox_buff
- jb init_attrlist_3 ;If list runs into the help
- inc no_help ; buffer, disable help
- push ax
- mov ax,helpbox_buff ;If past helpbox buffer, exit
- add ax,HELPBOX_BUFFSIZE
- cmp di,ax
- pop ax
- jb init_attrlist_3 ;If list past help box
- stc ; buffer, exit prog.
- jmp short init_attrlist_exit
- init_attrlist endp
-
- ;-----------------------------------------------------------------------------
- ; COMPUTE OFFSET Computes the offset into the attribute buffer for a
- ; given cursor location.
- ; Entry: DX - Row, Column of character
- ; Exit: CX - Offset in buffer.
- ;-----------------------------------------------------------------------------
- compute_offset proc near
- push ax
- push dx
- mov al,dh ;Copy column
- mul screen_cx ;Mul by width of screen
- xor dh,dh
- add ax,dx ;Add row
- xchg cx,ax
- pop dx
- pop ax
- ret
- compute_offset endp
-
- ;-----------------------------------------------------------------------------
- ; CHK INWIN Determines if a character is inside the bounds of an area
- ; Entry: BX - Pointer to bounding rectangle
- ; x1 db point 1 column
- ; y1 db point 1 row
- ; x2 db point 2 column
- ; y2 db point 2 row
- ; DX - Row, Column of character
- ; Exit: AL - <> 0 if inside area
- ;-----------------------------------------------------------------------------
- chk_inwin proc near
- push bx
- push cx
-
- push ax ;Save AX
- push dx ;Save current cursor pos
- call compute_box ;DX = UL corner, AX = LR corner
- pop bx
- xchg bx,dx ;DX = cur cursor, BX=UL corner
- mov cx,ax ;CX = LR corner
- pop ax ;Restore AX
-
- mov al,0 ;Clear inbox flag
-
- cmp dl,bl ;See if above starting row
- jb chk_inwin_exit
- cmp dh,bh ;See if left of starting col
- jb chk_inwin_exit
-
- cmp dl,cl ;See if below ending row
- ja chk_inwin_exit
- cmp dh,ch ;See if right of ending col
- ja chk_inwin_exit
- inc al
- chk_inwin_exit:
- pop cx
- pop bx
- ret
- chk_inwin endp
-
- ;-----------------------------------------------------------------------------
- ; FIND MIN Computes the smaller of two screen coordinates.
- ; Entry: AX - Row, Column of 1st coordinate
- ; BX - Pointer to 2nd coordinate
- ; Exit: AX - Result coordinate.
- ;-----------------------------------------------------------------------------
- find_min proc near
- cmp al,[bx]
- jbe find_min_1
- mov al,[bx]
- find_min_1:
- cmp ah,[bx+1]
- jbe find_min_2
- mov ah,[bx+1]
- find_min_2:
- ret
- find_min endp
-
- ;-----------------------------------------------------------------------------
- ; FIND MAX Computes the larger of two screen coordinates.
- ; Entry: DX - Row, Column of 1st coordinate
- ; BX - Pointer to 2nd coordinate
- ; Exit: AX - Result coordinate.
- ;-----------------------------------------------------------------------------
- find_max proc near
- cmp dl,[bx]
- jae find_max_1
- mov dl,[bx]
- find_max_1:
- cmp dh,[bx+1]
- jae find_max_2
- mov dh,[bx+1]
- find_max_2:
- ret
- find_max endp
-
- ;-----------------------------------------------------------------------------
- ; COMPUTE BOX Puts the starting row/column in DX and the SI and CX
- ; Entry: BX - Pointer to coordinates
- ; Exit: AX - Ending row/column
- ; DX - Starting row/column
- ;-----------------------------------------------------------------------------
- compute_box proc near
- mov ax,[bx]
- mov dx,[bx+2]
-
- cmp al,dl
- ja compute_box_1
- xchg al,dl
- compute_box_1:
- cmp ah,dh
- ja compute_box_2
- xchg ah,dh
- compute_box_2:
- ret
- compute_box endp
-
- ;-----------------------------------------------------------------------------
- ; SHOWHELP Displays a help screen on the first three lines of the display
- ;-----------------------------------------------------------------------------
- showhelp proc near
- cmp byte ptr no_help,0 ;See if help msg disabled.
- jne showhelp_exit
- mov dh,1 ;Box at top of screen
- mov cx,5
- mov di,helpbox_buff
- showhelp_1:
- push cx
- call saveline
- inc dh
- pop cx
- loop showhelp_1
-
- mov dh,1
- mov si,offset helpmsg1 ;Write help text line
- call writeline
- inc dh ;Move to next line
- mov si,offset helpmsg2
- call writeline
- inc dh ;Move to next line
- mov si,offset helpmsg3
- call writeline
- inc dh ;Move to next line
- mov si,offset helpmsg4
- call writeline
- inc dh ;Move to next line
- mov si,offset helpmsg5
- call writeline
-
- call getkey ;Wait for a key
- mov dh,1 ;Box at top of screen
- mov cx,5
- mov si,helpbox_buff
- showhelp_2:
- push cx
- call restoreline
- inc dh
- pop cx
- loop showhelp_2
- showhelp_exit:
- ret
- showhelp endp
-
- ;-----------------------------------------------------------------------------
- ; MSGBOX displays a message in a text window on the top line of the
- ; screen. The current data on the screen is saved.
- ;
- ; Entry: DS:SI - Pointer to string to display.
- ;-----------------------------------------------------------------------------
- msgbox proc near
- mov dh,0 ;Box at top of screen
- mov al,boxactive
- cmp al,2 ;Display sum only
- je msgbox_1
- or al,al ;If box already displayed,
- jne msgbox_1 ; don't save screen data.
- mov di,MSGBOX_BUFFER
- call saveline
- msgbox_1:
- mov si,offset program1
- mov cx,offset program2 - offset program1
- xor dx,dx
- msgbox_11:
- lodsb
- call writechar
- loop msgbox_11
- push dx
- msgbox_12:
- mov al,' ' ;Pad line with spaces
- call writechar
- cmp dl,screen_cx
- jb msgbox_12
- pop dx
-
- add dl,6
- mov si,offset summsg
- call writestr
- mov dl,screen_cx
- sub dl,12
- mov si,offset helptag
- call writestr
- msgbox_2:
- mov ah,text_attr
- mov si,offset overflowmsg ;Assume overflow
- cmp sum_overflow,0
- jne msgbox_error
- mov di,offset command_tail ;Point to num and print
- mov si,offset sum_num
- push di
- call hex2asc ;Convert number to ASCII
- pop si
- lodsb ;Get attribute for number
- mov ah,al
- msgbox_error:
- mov dl,44
- call writestr1 ;Write number or overflow
- msgbox_3:
- mov boxactive,1 ;Set box active flag
- ret
- msgbox endp
-
- ;-----------------------------------------------------------------------------
- ; CLEARBOX removes the title box from the screen.
- ;-----------------------------------------------------------------------------
- clearbox proc near
- cmp boxactive,0 ;If box already displayed,
- je clearbox_2 ; don't save screen data.
- mov si,MSGBOX_BUFFER
- mov dh,0 ;Box at top of screen
- call restoreline
- mov boxactive,0 ;Clear box displayed flag
- clearbox_2:
- ret
- clearbox endp
-
- ;-----------------------------------------------------------------------------
- ; WRITELINE Writes a line of help text to the screen. The line is padded
- ; with spaces to the right.
- ; Entry: DH - Line on screen to write
- ; SI - Pointer to ASCIIZ text
- ;-----------------------------------------------------------------------------
- writeline proc near
- push dx
- xor dl,dl ;Start at left side of screen
- call writestr ;Write string
- writeline_2:
- mov al,' ' ;Pad line with spaces
- call writechar
- cmp dl,screen_cx
- jb writeline_2
- pop dx
- ret
- writeline endp
-
- ;-----------------------------------------------------------------------------
- ; SAVELINE Saves the contents of a screen line ot a buffer
- ; Entry: DH - Line on screen to save
- ; DI - Pointer to save buffer
- ;-----------------------------------------------------------------------------
- saveline proc near
- push dx
- xor dl,dl ;Start at left side of screen
- xor cx,cx
- mov cl,screen_cx
- saveline_1:
- call getchar ;Read character from screen
- stosw
- inc dl ;Point to next character
- loop saveline_1
- pop dx
- ret
- saveline endp
-
- ;-----------------------------------------------------------------------------
- ; RESTORELINE Restores the screen that was covered by a line of program
- ; helptext.
- ; Entry: DH - Line on screen to restore
- ; SI - Pointer to buffer that contains original screen contents
- ;-----------------------------------------------------------------------------
- restoreline proc near
- push dx
- xor dl,dl ;Start at left side of screen
- xor cx,cx
- mov cl,screen_cx
- restoreline_1:
- lodsw
- call writechar1 ;Read character from screen
- loop restoreline_1
- pop dx
- ret
- restoreline endp
-
- ;-----------------------------------------------------------------------------
- ; WRITESTR Writes a string to the screen.
- ; Entry: DH,DL - Row/Column to write the string
- ; SI - Pointer to ASCIIZ text
- ;-----------------------------------------------------------------------------
- writestr proc near
- mov ah,text_attr
- writestr1:
- lodsb ;Read text from string, then
- or al,al ; call putchar to write to
- je writestr_1 ; the screen.
- call writechar1
- jmp short writestr1
- writestr_1:
- ret
- writestr endp
-
- ;-----------------------------------------------------------------------------
- ; WRITECHAR Writes a character to the screen
- ; Entry: AL - Character
- ; DX - Row, Column
- ;-----------------------------------------------------------------------------
- writechar proc near
- mov ah,text_attr
- writechar1:
- call putchar
- inc dl
- ret
- writechar endp
-
- ;-----------------------------------------------------------------------------
- ; HEX2ASC converts number in DX AX to ASCII
- ; Entry: SI - Pointer to number
- ; DI - Pointer to buffer to store ASCII number
- ;-----------------------------------------------------------------------------
- hex2asc proc near
- assume ds:code,es:nothing
- push bx
- push cx
- push si
- push bp
- push [si] ;Save current number
- push [si+2]
- push [si+4]
-
- mov al,number_attr ;Save proper attribute
- stosb
- test byte ptr [si+5],80h ;See if negative
- je hex_1
- call neg_number ;Negate number
- dec di
- mov al,negative_attr ;Change attribute to indicate
- mov ah,'-' ; negative number, then
- stosw ; print - sign.
- hex_1:
- xor cx,cx ;Clear digit counter
- hex_loop1:
- xor bx,bx ;BX used for zero test
- mov ax,[si+4] ;Get high word
- xor dx,dx ;Clear high word
- div base ;Divide by base
- mov [si+4],ax
- or bx,ax ;OR quotient for zero test
- mov ax,[si+2] ;Get mid word
- div base ;Divide by base
- mov [si+2],ax
- or bx,ax ;OR quotient for zero test
- mov ax,[si] ;Get low word
- div base ;Divide by base
- mov [si],ax
- or bx,ax ;OR quotient for zero test
-
- add dl,30h ;Convert to ascii
- push dx ;Save digit on stack
- inc cx ;Inc digit count
- or bx,bx
- jne hex_loop1 ;If number <> 0, continue.
-
- mov bl,"0" ;Set leading zero flag
- mov bh,3 ;Get comma spacing constant
-
- mov bp,cx ;Copy digit count
- xor ax,ax
- mov al,[si+6] ;Subtract exponent to get
- sub bp,ax ; num of non-fraction digits
- jmp short hex_2 ;Don't lead with a comma
- hex_loop2:
- xor ax,ax
- or ax,bp ;Get number non-fract digits
- js hex_4 ;If count neg, inside fract
- div bh ;If digit count a multiple
- or al,al ; of 3 insert comma.
- je hex_2
- or ah,ah
- jne hex_2
- mov al,','
- jmp short hex_3
- hex_2:
- or bp,bp ;If position count zero
- jne hex_4 ; insert decimal point.
- mov al,'.'
- hex_3:
- stosb ;Copy char to buffer
- hex_4:
- pop ax ;Get digit off stack
- or bl,al ;Don't print leading zeros.
- cmp bl,"0" ;The first non zero will
- je hex_5 ; change bl to non-zero.
- stosb
- hex_5:
- dec bp ;Dec current digit count
- loop hex_loop2
- cmp bl,"0" ;If number zero, write last
- jne hex_exit ; zero.
- mov al,bl
- stosb
- hex_exit:
- xor al,al ;Terminate with 0
- stosb
- pop [si+4] ;Restore number
- pop [si+2]
- pop [si]
- pop bp
- pop si
- pop cx
- pop bx
- ret
- hex2asc endp
-
- ;-----------------------------------------------------------------------------
- ; GETCHAR Reads a character and its attribute from the screen
- ; Entry: DH - Row of character to read
- ; DL - Column of character to read
- ; Exit: AL - Character
- ; AH - Attribute
- ;-----------------------------------------------------------------------------
- getchar proc near
- push bx
- cmp BIOSFlag,0
- jne getchar_bios
- push cx
- push si
- push ds
- call compute_offset ;Get offset into buffer
- shl cx,1 ;Double for char and attr
- lds si,video_ptr ;Get ptr to video memory
- add si,cx ;Double since char and attr
- lodsw ;Read char/attribute
- pop ds
- pop si
- pop cx
- jmp short getchar_exit
- getchar_bios:
- mov ah,2 ;Set cursor
- mov bh,screen_page
- int 10h
- mov ah,8 ;Read character/attr
- int 10h
- getchar_exit:
- pop bx
- ret
- getchar endp
-
- ;-----------------------------------------------------------------------------
- ; PUTCHAR Writes a character and its attribute to the screen
- ; Entry: AL - Character to write
- ; AH - Attribute to write
- ; DH - Row of character to write
- ; DL - Column of character to write
- ;-----------------------------------------------------------------------------
- putchar proc near
- push bx
- push cx
- push ax
- cmp BIOSFlag,0
- jne putchar_bios
- push di
- push es
- call compute_offset ;Get offset into buffer
- shl cx,1 ;Double since char and attr
- les di,video_ptr
- add di,cx ;Add to start of buffer
- stosw ;Read char/attribute
- pop es
- pop di
- jmp short putchar_exit
- putchar_bios:
- mov ah,2 ;Set cursor
- mov bh,screen_page
- int 10h
- pop ax
- push ax
- mov bl,ah ;Copy attribute
- mov ah,9 ;Read character/attr
- mov cx,1
- int 10h
- putchar_exit:
- pop ax
- pop cx
- pop bx
- ret
- putchar endp
-
- ;-----------------------------------------------------------------------------
- ; GETKEY Waits for a key from the keyboard.
- ; Exit: AX - Scan code, ASCII char from keyboard.
- ;-----------------------------------------------------------------------------
- getkey proc near
- mov ah,1 ;Check for key
- int 16h
- jnz getkey_exit
- int 28h ;Call DOS Idle
- mov ax,1680h ;Release Timeslice
- int 2fh
- jmp short getkey
- getkey_exit:
- xor ax,ax ;Get key
- int 16h
- ret
- getkey endp
- even ;Align stack on word boundry
- end_of_resident = $
-
- ;----------------------------------------------------------------------------
- ; Non-resident data.
- ;----------------------------------------------------------------------------
- alrdy_installed db 0 ;Installed flag
- installed_seg dw 0 ;Segment of installed code
- dos_version dw 0 ;DOS version
-
- patchcode db "AlLs"
- ShiftCodes db "Rs","Ls","Al","Ct" ;These codes are used by
- ShiftText db "Ctrl",0 ; PATCH.COM for indicating
- db "Alt",0 ; Hot Shift combinations.
- db "Left-Shift",0
- db "Right-Shift",0
-
- infomsg2 db "ADDIT uninstalled$"
-
- errmsg0 db "Need DOS 3.0 or greater$"
- errmsg1 db "ADDIT not installed$"
- errmsg2 db "Usage: ADDIT [/B][/U]",13,10
- db "/B = Use Video BIOS",13,10
- db "/U = Uninstall",13,10,"$"
- errmsg3 db "Can",39,"t uninstall$"
- errmsg4 db "ADDIT already installed$"
- errmsg5 db "Can not find Critical error flag$"
- endmsg db 13,10,"$"
-
- infomsg1 db "ADDIT installed",13,10,10
- db "Hot key is "
- infomsg1a db "$"
-
- ;----------------------------------------------------------------------------
- ; Initialization routine.
- ;----------------------------------------------------------------------------
- initialize proc near
- assume cs:code,ds:code,es:code
- cld
- mov dx,offset program ;Print copyright message
- call printmsgcr
-
- mov ah,30h ;Get DOS version
- int 21h
- xchg al,ah ;Swap major, minor numbers
- mov dx,offset errmsg0 ;Bad DOS version
- cmp ah,3 ;Run if DOS 3.0 or greater.
- jb disp_error
- mov dos_version,ax ;Save version number
-
- mov ax,offset end_of_code+512 ;Set stack ptr
- mov sp,ax
- add ax,15
- mov cl,4 ;Convert offset to segment size
- shr ax,cl
- mov ah,4ah ;Reduce memory allocation
- int 21h
-
- call find_installed ;See if already installed
- jc init_1
- inc alrdy_installed ;Yes, set flag
- mov installed_seg,es ;Save seg of installed code
- init_1:
- push ds
- pop es
- mov dx,offset errmsg4 ;Default message
- mov di,80h ;Parse command line
- xor cx,cx
- or cl,[di] ;Get length of cmd line
- je init_exit
- init_2:
- mov al,'/'
- repne scasb ;Find command line switches
- jne init_exit
- mov al,[di] ;Get comamnd line switch
- or al,20h
- cmp al,'b' ;See if Video BIOS parameter
- jne init_3
- inc BIOSFlag
- jmp short init_2
- init_3:
- cmp al,'u' ;See if uninstall
- je init_4
- mov dx,offset errmsg2 ;Print useage statement
- ;
- ;Display error message.
- ;
- assume ds:nothing
- disp_error:
- push cs
- pop ds
- assume ds:code
- call printmsgcr ;print string
-
- mov ax,4c01h ;Terminate with RC = 1
- int 21h
- init_4:
- call remove ;Remove installed copy
- jc disp_error
- jmp short exit
- init_exit:
- cmp alrdy_installed,0
- jne disp_error
- call install
- jc disp_error
- exit:
- mov ax,4C00h ;Terminate with RC = 0
- int 21h
- initialize endp
-
- ;-----------------------------------------------------------------------------
- ; INSTALL Installs the program
- ;-----------------------------------------------------------------------------
- assume cs:code,ds:code,es:code
- install proc near
- mov ah,34h ;Get ptr to INDOS flag
- int 21h
- mov word ptr indos_ptr,bx
- mov word ptr indos_ptr[2],es
- call findCEF ;Get ptr to crit error flag
- jc install_error
- mov word ptr criterr_ptr,bx
- mov word ptr criterr_ptr[2],es
- mov al,08h ;Get/set the timer interrupt
- mov dx,offset timerint
- mov di,offset int08h
- call set_interrupt
- mov al,09h ;Get/set the keyboard int
- mov dx,offset keyint
- mov di,offset int09h
- call set_interrupt
- mov al,10h ;Get/set the video interrupt
- mov dx,offset videoint
- mov di,offset int10h
- call set_interrupt
- mov al,13h ;Get/set the disk interrupt
- mov dx,offset diskint
- mov di,offset int13h
- call set_interrupt
- mov al,28h ;Get/set the DOS idle int
- mov dx,offset idleint
- mov di,offset int28h
- call set_interrupt
-
- push cs
- push cs
- pop ds
- assume ds:code
- pop es
- assume es:code
- call setshiftmsg ;Set proper install text
- mov dx,offset infomsg1 ;Print program installed msg
- call printmsgcr
-
- mov dx,ATTR_BUFFER ;Set pointers for resident
- add dx,attr_buffsize ; code.
- mov helpbox_buff,dx
- add dx,HELPBOX_BUFFSIZE + 512
- mov res_stack,dx
- add dx,15
- mov cl,4
- shr dx,cl
- mov ax,3100h ;Terminate and stay resident
- int 21h
- install_error:
- ret
- install endp
-
- ;-----------------------------------------------------------------------------
- ; REMOVE uninstalls the installed program from memory.
- ;-----------------------------------------------------------------------------
- remove proc near
- assume ds:code,es:code
- push ds
- push es
-
- mov dx,offset errmsg1 ;Not installed message
- cmp alrdy_installed,0
- je remove_error1
-
- mov ds,installed_seg ;Point DS to installed code
- assume ds:nothing
-
- mov al,8 ;Restore int 8 (Timer)
- mov dx,offset timerint
- mov di,offset int08h
- call restore_int
- jc remove_error
- mov al,9 ;Restore int 9 (keyboard)
- mov dx,offset keyint
- mov di,offset int09h
- call restore_int
- jc remove_error
- mov al,10h ;Restore int 10h (BIOS Video)
- mov dx,offset videoint
- mov di,offset int10h
- call restore_int
- jc remove_error
- mov al,13h ;Restore int 13h (BIOS disk)
- mov dx,offset diskint
- mov di,offset int13h
- call restore_int
- jc remove_error
- mov al,28h ;Restore int 28h (DOS Idle)
- mov dx,offset idleint
- mov di,offset int28h
- call restore_int
- jc remove_error
- mov es,ds:[2ch] ;Get installed env seg
- mov ah,49h
- int 21h ;Free installed env segment
- push ds
- pop es
- mov ah,49h ;Free installed program segment
- int 21h
- mov ax,cs
- mov ds,ax
- mov es,ax
- mov dx,offset infomsg2 ;Print program removed msg
- call printmsgcr
- clc
- remove_exit:
- pop ds
- pop es
- ret
- remove_error:
- mov dx,offset errmsg3 ;Can't uninstall msg
- remove_error1:
- stc
- jmp short remove_exit
- remove endp
-
- ;-----------------------------------------------------------------------------
- ; SETINTERRUPT Get and sets an interrupt
- ; Entry: AL - Interrupt number
- ; DX - Pointer to new interrupt routine
- ; DI - Pointer to storage location for old interrupt vector
- ;-----------------------------------------------------------------------------
- assume cs:code,ds:code,es:nothing
- set_interrupt proc near
- push es
- push ax
- mov ah,35h ;DOS get interrupt
- int 21h
- pop ax
- mov word ptr [di],bx ;Save old vector
- mov word ptr [di+2],es
- mov ah,25h ;DOS set interrupt
- int 21h
- pop es
- ret
- set_interrupt endp
-
- ;-----------------------------------------------------------------------------
- ; RESTOREINT Checks to see if an interrupt vector has been changed, if not
- ; the interrupt vector is restored with its original value
- ; Entry: AL - Interrupt number
- ; DS:DX - Pointer to current interrupt routine
- ; DS:DI - Pointer to old interrupt vector
- ;-----------------------------------------------------------------------------
- assume cs:code,ds:nothing
- restore_int proc near
- push es
- push ax
- mov ah,35h ;DOS get interrupt
- int 21h
- pop ax ;Get back interrupt number
- cmp dx,bx ;Compare routine offset
- jne restoreint_error
- mov bx,es ;Get current vector segment
- mov cx,ds ;Get installed segment
- cmp cx,bx ;Compare routine segment
- jne restoreint_error
- push ds
- lds dx,ds:[di] ;Get old vector
- mov ah,25h ;DOS set interrupt
- int 21h
- clc
- pop ds
- restoreint_exit:
- pop es
- ret
- restoreint_error:
- stc
- jmp short restoreint_exit
- restore_int endp
-
- ;-----------------------------------------------------------------------------
- ; FINDCEF Finds the DOS ErrorMode (Critical error) flag
- ; Exit: ES:BX - Segment,offset of ErrorMode flag
- ; CF - Clear if flag found
- ;-----------------------------------------------------------------------------
- findCEF proc near
- mov ah,34h ;Get InDOS address
- int 21h
- dec bx
- cmp dos_version,30ah ;If DOS 3.1 or later, ErrorMode
- jnc findCEF_exit ; sits before InDOS.
-
- mov ax,3e80h ;CMP opcode
- mov si,028cdh ;Int 28 Opcode
- mov dl,75h ;JNE Opcode
- mov cx,-1 ;max search length
- mov di,bx ;start at INDOS address
- findCEF_1:
- repne scasb ;do the search
- jcxz findCEF_notfound ;branch if search failed
- cmp es:[di],ah ;Check other half of CMP opcode
- jne findCEF_1
- cmp byte ptr es:[di+4],dl ;Check for JNE
- jne findCEF_1
- cmp word ptr es:[di+6],si ; Check for Int 28h call
- jne findCEF_1 ;Resume loop if not found
- inc di
- mov bx,es:[di] ;Get offset of ErrorMode flag
- clc
- findCEF_exit:
- ret
- findCEF_notfound:
- stc
- mov dx,offset errmsg5 ;Can't find Critical Error flg
- jmp short findCEF_exit
- findCEF endp
-
- ;-----------------------------------------------------------------------------
- ; FIND INSTALLED Find the installed code by scanning the memory control blocks.
- ; Exit: AX - Segment of installed code if found.
- ; CF - Clear if installed code found
- ;-----------------------------------------------------------------------------
- find_installed proc near
- assume ds:code,es:code
- mov word ptr prog,0
- mov bx,0A000h ;Start at upper mem blk start
- mov ax,cs ;keep CS value in AX
- find_installed_1:
- inc bx ;increment search segment value
- mov es,bx
- assume es:nothing
- cmp ax,bx ;not installed if current
- je find_installed_2 ; segment is found.
- call cmpheader
- jne find_installed_1 ;loop back if not found
-
- clc
- find_installed_exit:
- ret
- find_installed_2:
- stc
- jmp short find_installed_exit
- find_installed endp
-
- ;-----------------------------------------------------------------------------
- ; CMPHEADER compares the first 16 bytes of this file with the segment
- ; pointed to by ES.
- ; Entry: DS - code segment
- ; ES - pointer to segment to compare
- ; Exit: ZF - 0 = segments match.
- ;-----------------------------------------------------------------------------
- cmpheader proc near
- assume ds:code,es:nothing
- mov si,offset prog ;Search this segment for ASCII
- mov di,si ; fingerprint.
- mov cx,16
- repe cmpsb
- ret
- cmpheader endp
-
- ;-----------------------------------------------------------------------------
- ; SETSHIFTMSG Sets the proper hot shift text from the code set by PATCH.COM
- ;-----------------------------------------------------------------------------
- setshiftmsg proc near
- assume ds:code,es:code
- mov si,offset infomsg1a
- mov ax,word ptr patchcode
- call setshiftmsg1
- mov ax,word ptr [patchcode+2]
- call setshiftmsg1
- mov byte ptr [si],'$'
- ret
- setshiftmsg endp
-
- setshiftmsg1 proc near
- mov byte ptr [si],'<'
- inc si
- mov di,offset shiftcodes ;Scan code list to find
- mov cx,4 ; the proper shift word
- repne scasw ; to use in the message
- jne setshiftmsg_exit
- mov ah,cl
- mov di,offset shifttext ;Find message in list
- xor al,al
- or ah,ah
- je setshiftmsg_2
- setshiftmsg_1:
- mov cx,30
- repne scasb
- dec ah
- jne setshiftmsg_1
- setshiftmsg_2:
- xchg di,si
- setshiftmsg_3:
- lodsb ;Copy shift label to msg
- stosb
- or al,al
- jne setshiftmsg_3
- mov byte ptr [di-1],'>' ;Append closing >
- mov si,di
- setshiftmsg_exit:
- ret
- setshiftmsg1 endp
-
- ;-----------------------------------------------------------------------------
- ; PRINTMSG prints the message pointed to by DX to the screen.
- ; Entry: DX - pointer to ASCII message terminated by $
- ;-----------------------------------------------------------------------------
- printmsg proc near
- assume ds:nothing,es:nothing
- push ds
- push cs
- pop ds
- assume ds:code
- mov ah,9 ;Print message
- int 21h
- pop ds
- ret
- printmsg endp
-
- ;-----------------------------------------------------------------------------
- ; PRINTMSGCR calls PRINTMSG, then appends a carriage return to the message.
- ; Entry: DX - pointer to ASCII message terminated by $
- ;-----------------------------------------------------------------------------
- printmsgcr proc near
- assume ds:nothing,es:nothing
- push dx
- call printmsg
- mov dx,offset endmsg
- call printmsg
- pop dx
- ret
- printmsgcr endp
- even
- end_of_code = $
- code ends
-
- end prog